home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / brklyprl.lha / Comp / helpinfo.pl < prev    next >
Text File  |  1989-04-14  |  2KB  |  54 lines

  1.  
  2. /* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
  3.  
  4. /* Copyright Herve' Touati, Aquarius Project, UC Berkeley */
  5.  
  6. % Help information.
  7. % Invoked by the command help or help(option).
  8.  
  9. help :-
  10.     nl,
  11.     write('The compiler is called as plm(filename) or plm(filename,optionlist).'),nl,
  12.     write('The options in optionlist must be a subset of '),
  13.     help_optionlist(OptList),
  14.     write(OptList), write('.'), nl,
  15.     write('Call help(option) for further information on an option.'),nl.
  16.     
  17.  
  18. help(Option) :-
  19.     nl,
  20.     nonvar(Option),
  21.     help_info(Option, String), 
  22.     put(9),write(String), nl,
  23.     fail.
  24. help(Option) :-
  25.     help_optionlist(OptList),
  26.     (\+(help_member(Option,OptList)); var(Option)),
  27.     put(9),write('The option '''),write(Option),write(''' is unknown.'),nl,
  28.     put(9),write('The known options are in the set '),
  29.     write(OptList), write('.'),nl.
  30. help(_).
  31.  
  32. help_optionlist([a,l,s,u,q,a(_)]).
  33.  
  34. help_info(a, 'Compile an allocate instruction without arguments.').
  35. help_info(a, 'The default is to use a single-argument allocate with the').
  36. help_info(a, 'environment size as argument.').
  37. help_info(l, 'Write the output in Prolog-readable list form.').
  38. help_info(l, 'The default is to write the output in human-readable form.').
  39. help_info(u, 'Do not expand calls of is/2 into calls of is/4.').
  40. help_info(u, 'The default is to expand is/2 into is/4 whenever it is possible.').
  41. help_info(u, 'Option u overrides option s.').
  42. help_info(q, 'When output is in human-readable form, quote all atoms.').
  43. help_info(q, 'The default is to quote only those atoms that need it.').
  44. help_info(q, 'Option q has no effect when option l (Prolog-readable form) is used.').
  45. help_info(a(X), 'The parameter of a(_) (which must be atomic) is appended to all').
  46. help_info(a(X), 'labels in the human-readable code.  The default is to append nothing.').
  47. help_info(s, 'Compile the operators +, -, \/, /\ in an expression as builtins,').
  48. help_info(s, 'and only the others with is/4.  The default is to compile all').
  49. help_info(s, 'operators with is/4.').
  50. help_info(s, 'Option s has no effect when option u (unexpanded expression) is used.').
  51.  
  52. help_member(X, [X|_]).
  53. help_member(X, [_|L]) :- help_member(X, L).
  54.